NewGridFloatFromESRI_ASCII Subroutine

private subroutine NewGridFloatFromESRI_ASCII(fileName, layer)

Uses

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileName

file to read

type(grid_real), intent(out) :: layer

returned grid float


Variables

Type Visibility Attributes Name Initial
real(kind=double), public :: corner
character(len=50), public :: dummy
integer(kind=short), public :: fileUnit
integer(kind=short), public :: i
integer(kind=short), public :: ios
integer(kind=short), public :: j

Source Code

SUBROUTINE NewGridFloatFromESRI_ASCII &
!
(fileName, layer)

USE Utilities, ONLY: &
!Imported routines:
GetUnit

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(in) :: fileName  !! file to read

!Arguments with intent(out)
TYPE (grid_real), INTENT (OUT) :: layer !!returned grid float

!Local variables:
INTEGER (KIND = short)          :: fileUnit
INTEGER (KIND = short)          :: ios
CHARACTER (LEN = 50)            :: dummy
INTEGER (KIND = short)          :: i, j
REAL (KIND = double)            :: corner
!------------end of declaration------------------------------------------------

!open file
fileUnit = GetUnit ()
OPEN (UNIT = fileUnit, file = fileName, STATUS = 'OLD', IOSTAT = ios)
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error opening file: ',    &
              code = openFileError, argument = fileName )
END IF

!read number of columns
READ (fileUnit,*,IOSTAT = ios) dummy, layer % jdim
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error reading columns in file: ',    &
              code = genericIOError, argument = fileName )
END IF

!read number of rows
READ (fileUnit,*,IOSTAT = ios) dummy, layer % idim
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error reading rows in file: ',    &
              code = genericIOError, argument = fileName )
END IF

!read xll corner
READ (fileUnit,*,IOSTAT = ios) dummy, corner
layer % xllcorner = corner
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error reading xll in file: ',    &
              code = genericIOError, argument = fileName )
END IF

!read yll corner
READ (fileUnit,*,IOSTAT = ios) dummy, corner
layer % yllcorner = corner
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error reading yll in file: ',    &
              code = genericIOError, argument = fileName )
END IF

!read cellsize
READ (fileUnit,*,IOSTAT = ios) dummy, layer % cellsize
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error reading cellsize in file: ',    &
              code = genericIOError, argument = fileName )
END IF

!read nodata value
READ (fileUnit,*,IOSTAT = ios) dummy, layer % nodata
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error reading missing value in file: ',    &
              code = genericIOError, argument = fileName )
END IF

!allocate grid
ALLOCATE ( layer % mat (layer % idim, layer % jdim), STAT = ios )
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',  &
             'memory allocation ',  &
             code = memAllocError,argument = fileName )
ENDIF

!read data
DO i = 1,layer % idim
  READ (fileUnit,*) ( layer % mat (i,j) , j = 1,layer % jdim )
END DO

CLOSE (fileUnit)

!Set to default other fields
layer % standard_name = ''
layer % long_name = ''
layer % units = ''
layer % varying_mode = 'sequence' 
layer % valid_min = layer % nodata
layer % valid_max = layer % nodata
layer % esri_pe_string = ''
layer % reference_time = timeDefault
layer % current_time = timeDefault
layer % next_time = timeDefault

END SUBROUTINE NewGridFloatFromESRI_ASCII